home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
prolog
/
ai.prl
/
dprolog.lha
/
dprolog.ari
(
.txt
)
< prev
next >
Wrap
Microsoft Windows Help File Content
|
1991-03-05
|
30KB
|
630 lines
:- write($
d-Prolog - Arity Version 1.2
Copyright (C) 1988 Donald Nute
Advanced Computational Methods Center
University of Georgia, Athens, GA 30602
reset_op,
op(1100,fx,@),
op(1100,fx,@@),
op(900,fx,neg ),
op(1100,xfy,:=),
op(1100,xfy,:^),
op(200,fx,list).
/***********************************************************************
* *
* The clause 'true' is defeasibly derivable. This is the termin- *
* ating condition for defeasible derivability. *
* *
***********************************************************************/
defeasibly_derivable(true,_):- !.
/***********************************************************************
* *
* A conjunction is defeasibly derivable if both conjuncts are. *
* *
***********************************************************************/
defeasibly_derivable((First,Rest),Clause):-
!,
defeasibly_derivable(First,Clause),
defeasibly_derivable(Rest,Clause).
/***********************************************************************
* *
* Indefeasibly derivable goals are also defeasibly derivable. *
* *
***********************************************************************/
defeasibly_derivable(Goal,_):-
Goal.
/***********************************************************************
* *
* A goal is defeasibly derivable if it is the consequent of a de- *
* feasible rule whose antecedent is defeasibly derivable and which *
* is not defeated by any competing rule or defeater. *
* *
***********************************************************************/
defeasibly_derivable(Goal,_):-
(Goal := Condition),
defeasibly_derivable(Condition,Goal),
not defeat(Goal,Condition).
/***********************************************************************
* *
* A goal is defeasibly derivable if a contrary is not indefeasibly *
* derivable and it is the consequent of an indefeasibly rule whose *
* consequent is defeasibly derivable. *
* *
***********************************************************************/
defeasibly_derivable(Goal,_):-
clause(Goal,Condition),
Condition\=true,
defeasibly_derivable(Condition,Goal),
not Condition,
contrary(Goal,Contrary),
not Contrary.
/***********************************************************************
* *
* We defeat a rule with consequent Head and condition Body if there *
* is a contrary of Head that defeats the rule. *
* *
***********************************************************************/
defeat(Head,Body):-
contrary(Head,Contrary),
defeat(Head,Body,Contrary),
!.
/***********************************************************************
* *
* A defeasible rule is always defeated by any indefeasibly deriv- *
* able contrary of its consequent. *
* *
***********************************************************************/
defeat(Head,Body,ContraryOfHead):-
ContraryOfHead,
!.
/***********************************************************************
* *
* Next we look for a defeasible rule with a consequent that is a *
* contrary of the consequent of the defeasible rule we are trying *
* to defeat. We compare the condition of this competing rule with *
* the body of the rule we are trying to defeat. For the competing *
* rule to defeat the original rule, the antecedent of the competing *
* rule must be defeasibly derivable and must not be less informa- *
* tive than the antecedent of the original rule. *
* *
***********************************************************************/
defeat(Head,Body,ContraryOfHead):-
(ContraryOfHead:=Condition),
not_more_informative(Body,Condition,Head,ContraryOfHead),
defeasibly_derivable(Condition,ContraryOfHead),
!.
/***********************************************************************
* *
* This is exactly like the last procedure except that we try to use *
* a defeater to defeat the rule. *
* *
***********************************************************************/
defeat(Head,Body,ContraryOfHead):-
(ContraryOfHead:^Condition),
not_more_informative(Body,Condition,Head,ContraryOfHead),
defeasibly_derivable(Condition,ContraryOfHead),
!.
/***********************************************************************
* *
* One last way a rule may be defeated by a contrary of itss conse- *
* quent is if the contrary is the consequent of some indefeasible *
* rule whose antecedent is defeasibly derivable. *
* *
***********************************************************************/
defeat(Head,Body,ContraryOfHead):-
functor(ContraryOfHead,Predicate,_),
not system(Predicate),
clause(ContraryOfHead,Condition),
defeasibly_derivable(Condition,ContraryOfHead).
/***********************************************************************
* *
* We want to know if one set of clauses is more informative than *
* another set of clauses. We need this to decide which of two com- *
* peting rules to use. We also keep track of the consequents of *
* the competing rules so we know what to tell the user if we find *
* a d-Prolog syntax error. *
* *
* Clauses2 is not more informative than Clauses1 if we can not de- *
* rive Clauses1 from Clauses2 using only our absolute rule. *
* *
***********************************************************************/
not_more_informative(Clauses1,Clauses2,Clause1,Clause2):-
not relcon(Clauses2,Clauses1,Clause2,Clause1),
!.
/***********************************************************************
* *
* Clauses2 also is not more informative than Clauses1 if we can de- *
* rive Clauses2 from Clauses1 using only our absolute rule. *
* *
***********************************************************************/
not_more_informative(Clauses1,Clauses2,Clause1,Clause2):-
relcon(Clauses1,Clauses2,Clause1,Clause2).
/***********************************************************************
* *
* A set of goals are relevant consequents of a set of premises *
* (relative to a database) iff it is possible to derive all of the *
* goals from the set of premises using only the indefeasible rules *
* in the database. That is, no facts or defeasible rules may be *
* used. *
* *
* The clause 'true' is a relevant consequence of anything. *
* *
***********************************************************************/
relcon(true,_,_,_):- !.
/***********************************************************************
* *
* If the condition of the rule is a disjunction, then there is a *
* disjunction error in the rule. d-Prolog will not compare the *
* conditions of rules if one of the conditions includes disjunc- *
* tions. We need to know the clause that is the head of the rule *
* when this happens so we will know what to tell the user. *
* *
***********************************************************************/
relcon((_;_),_,Clause,_):-
disjunction_error(Clause).
relcon(_,(_;_),_,Clause):-
disjunction_error(Clause).
/***********************************************************************
* *
* A conjunction is a relevant consequence of some set of premises if *
* each conjunct is a relevant consequence *
* *
***********************************************************************/
relcon((First,Rest),Premises,Clause1,Clause2):-
!,
relcon(First,Premises,Clause1,Clause2),
relcon(Rest,Premises,Clause1,Clause2).
/***********************************************************************
* *
* A clause with a system predicate is a relevant consequence just in *
* case it succeeds. *
* *
***********************************************************************/
relcon(Goal,_,_,_):-
functor(Goal,Predicate,_),
system(Predicate),
!,
Goal.
/***********************************************************************
* *
* Every member of the temporary set of premises is a relevant con- *
* sequence. *
* *
***********************************************************************/
relcon(Goal,Premises,_,Clause):-
belongs(Goal,Premises,Clause),
!.
/***********************************************************************
* *
* If a clause in the consequent of any indefeasible rule in the *
* database, then it is a relevant consquence of the temporary pre- *
* mise set if the antecedent of that rule is a set of relevant con- *
* sequences of the temporary premise set. *
* *
***********************************************************************/
relcon(Goal,Premises,_,Clause):-
clause(Goal,Body),
Body\=true,
relcon(Body,Premises,Goal,Clause),
!.
/***********************************************************************
* *
* The conmplement of any clause is a contrary of that clause. Any *
* two clauses which are incompatible are contraries of each other. *
* We use the notion of the contrary of a clause in testing to see *
* is a rule is defeated. *
* *
***********************************************************************/
contrary(Clause1,Clause2):-
incompatible(Clause1,Clause2).
contrary(Clause1,Clause2):-
incompatible(Clause2,Clause1).
contrary(Clause1,Clause2):-
comp(Clause1,Clause2).
/***********************************************************************
* *
* The complement of an atomic formula is its negation. The comple- *
* ment of a negative literal is the atomic formula negated in the *
* literal. *
* *
***********************************************************************/
comp(neg Atom,Atom):-
!.
comp(Atom,neg Atom).
/***********************************************************************
* *
* The predicate belongs succeeds if its second argument is a con- *
* junction and its first argument is a conjunct in the conjunction. *
* This predicate will call the disjunction error routine if it de- *
* tects a disjunction in a clause being examined. The third argu- *
* ment of belongs passes the original clause that originated the *
* disjunctive search for the proposed conjunct. This information *
* will be needed if the disjunction error routine is invoked. *
* *
***********************************************************************/
belongs(_,(_;_),Clause):-
disjunction_error(Clause).
belongs(Clause,Clause,_):- !.
belongs(Clause,(Clause,_),_):- !.
belongs(Clause1,(_,Rest),Clause2):-
!,
belongs(Clause1,Rest,Clause2).
/***********************************************************************
* *
* We invoke the d-Prolog inference engine by using the defeasible *
* query operator @ in front of our goal. *
* *
***********************************************************************/
@ Goal:- defeasibly_derivable(Goal,[]).
/***********************************************************************
* *
* We use the predicate @@ as a way of asking d-Prolog to make a com- *
* plete investigation of a goal. A complete query will tell whe- *
* a goal or any contrary of the goal is either absolutely or defeas- *
* ibly derivable. *
* *
***********************************************************************/
@@ Goal:-
improper(Goal),
write('Improper argument for @@.'),
nl,
write('Argument may not contain a variable, ;, ! or not.'),
nl,
!,
fail.
@@ Goal:-
Goal,
!,
write('definitely, yes -'),
nl,
contrary(Goal,Contrary),
Contrary,
write('and definitely, no - contradictory'),
nl.
@@ Goal:-
contrary(Goal,Contrary),
Contrary,
!,
write('definitely, no - '),
nl.
@@ Goal:-
defeasibly_derivable(Goal,[]),
!,
write('presumably, yes -'),
nl,
contrary(Goal,Contrary),
defeasibly_derivable(Contrary,[]),
write('and presumably, no - weakly contradictory'),
nl.
@@ Goal:-
contrary(Goal,Contrary),
defeasibly_derivable(Contrary,[]),
!,
write('presumably, no -'),
nl.
@@ Goal:-
write('can draw no conclusion'),
nl.
/***********************************************************************
* *
* The complete query operator @@ is to be used only for goals which *
* contain no variables. A goal with a variable is an improper argu- *
* ment for @@. Any goal containing a cut, not, or a disjunction is *
* also improper. *
* *
***********************************************************************/
improper('!').
improper((not _)) :- !.
improper((_;_)):- !.
improper((First,_)):-
improper(First),
!.
improper((_,Rest)):-
!,
improper(Rest).
improper(Clause):-
Clause =.. [Predicate|ArgumentList],
member(Argument,ArgumentList),
var(Argument).
/***********************************************************************
* *
* The predicate member succeeds if its second argument is a list *
* and is first argument is a member of that list. *
* *
***********************************************************************/
member(X,[X|_]).
member(X,[_|Y]):-
member(X,Y).
/***********************************************************************
* *
* When we list a predicate, we also want to see the defeasible rules *
* and defeaters for this predicate, any rules or defeaters for the *
* negation of this predicate, and any clauses incompatible with *
* clause containing this predicate. The list operation provides *
* this information. *
* *
***********************************************************************/
list(Predicate):-
listing(Predicate),
fail.
list(Predicate):-
clause(neg Atom,Body),
functor(Atom,Predicate,_),
pprint(neg Atom,' :-',Body),
fail.
list(Predicate):-
(Head := Body),
functor(Head,Predicate,_),
pprint(Head,' :=',Body),
fail.
list(Predicate):-
((neg Atom) := Body),
functor(Atom,Predicate,_),
pprint(neg Atom,' :=',Body),
fail.
list(Predicate):-
(Head :^ Body),
functor(Head,Predicate,_),
pprint(Head,' :^',Body),
fail.
list(Predicate):-
((neg Atom) :^ Body),
functor(Atom,Predicate,_),
pprint(neg Atom,' :^',Body),
fail.
list(Predicate):-
incompatible(Clause1,Clause2),
functor(Clause1,Predicate,_),
write('incompatible('),
write(Clause1),
write(','),
write(Clause2),
write(').'),
nl,
fail.
list(Predicate):-
incompatible(Clause1,Clause2),
functor(Clause2,Predicate,_),
write('incompatible('),
write(Clause2),
write(','),
write(Clause1),
write(').'),
nl,
fail.
list(_).
/***********************************************************************
* *
* The pprint procedure pretty-prints rules for us. It is an essen- *
* tial subroutine of the list procedure. The pprint procedure has *
* components, one of arity 3, one of arity 2, and one of arity 1. *
* The component of arity 3 take the head, operator, and body of a *
* rule as arguments, writes the head, and passes the operator and *
* body to the component of arity 2. The component of arity 2 writes *
* the operator of the rule, then terminates pretty-printing in an *
* appropriate way if the body of the rule is the special predicate *
* true. If the body of the rule is anything else, this component *
* passes the body of the rule along to the component of arity 1 for *
* pretty-printing. *
* *
***********************************************************************/
pprint(Head,Operator,Body):-
!,
write(Head),
pprint(Operator,Body).
/***********************************************************************
* *
* The next clause completes the pretty-printing of a negative fact *
* by printing a period. The only kind of rule list will pass to *
* pprint that has :- as operator and true as body is a negative *
* fact. *
* *
***********************************************************************/
pprint(' :-',true):-
!,
write(' .'),
nl.
pprint(' :-',Clause):-
!,
write(' :-'),
pprint(Clause).
/***********************************************************************
* *
* The next clause processes a defeasible rule or defeater with an *
* empty antecedent, i.e., with the special predicate true as its *
* body. It indents and prints 'true', then finishes by printing a *
* period. *
* *
***********************************************************************/
pprint(Operator,Clause):-
write(Operator),
Clause==true,
!,
nl,
write(' true.'),
nl.
pprint(Operator,Clause):-
pprint(Clause).
/***********************************************************************
* *
* The arity 1 component of pprint breaks a conjunction into its in- *
* vidual conjuncts, then prints each conjunct in a suitable format. *
* *
***********************************************************************/
pprint((First,Rest)):-
!,
nl,
write(' '),
write(First),
write(' ,'),
pprint(Rest).
pprint(Clause):-
nl,
write(' '),
write(Clause),
write(' .'),
nl.
/***********************************************************************
* *
* The predicate rescind is a d-Prolog counterpart of the Prolog *
* predicate retractall. Besides ordinary Prolog rules, it also *
* removes all negations, defeasible rules and defeaters from the *
* database. *
* *
***********************************************************************/
rescind(Clause):-
retractall(Clause),
retractall((neg Clause)),
retractall((:-(Clause,_))),
retractall((:-(neg Clause,_))),
retractall((:=(Clause,_))),
retractall((:=(neg Clause,_))),
retractall((:^(Clause,_))),
retractall((:^(neg Clause,_))).
retractall(Clause):-
retract(Clause),
fail.
retractall(_).
/***********************************************************************
* *
* The syntax of d-Prolog does not allow disjunctions. Otherwise, *
* the relcon test would require too much computation. It is left *
* to the d-Prolog programmer to write programs that do not use dis- *
* junction. If the d-Prolog inference engine encounters a disjunc- *
* tion at a crucial point in its computation, it will invoke the *
* disjunction_error procedure defined below. This routine will *
* locate all disjunction errors for the goal that invoked the dis- *
* jundtion error procedure and display them. *
* *
***********************************************************************/
disjunction_error(Clause):-
nl,
write('d-Prolog Syntax Error'),
nl,
nl,
clause(Clause,Body),
bad_syntax(Body),
pprint(Clause,' :-',Body),
fail.
disjunction_error(Clause):-
nl,
(Clause := Body),
bad_syntax(Body),
pprint(Clause,' :=',Body),
fail.
disjunction_error(Clause):-
nl,
(Clause :^ Body),
bad_syntax(Body),
pprint(Clause,' :^',Body),
fail.
disjunction_error(_):-
write(
'This clause contains an illegal disjunction. Evaluation aborted.'
),
nl,
abort.
/***********************************************************************
* *
* The following procedure is used by the disjunction_error routine *
* to determine whether a clause contains a disjunction. *
* *
***********************************************************************/
bad_syntax((_;_)) :- !.
bad_syntax(((_;_),_)) :- !.
bad_syntax((_,Rest)):-
!,
bad_syntax(Rest).
/***********************************************************************
* *
* The following procedures will reconsult a d-Prolog database with- *
* out losing defeasible rules, defeaters, or negative rules that are *
* divided because they have different d-Prolog predicates. This *
* facility expects the d-Prolog database to be on the selected disk *
* and to have the .DPL extension. The parameter passed to reload *
* should be the name of the file without any extension. *
* *
***********************************************************************/
reload(Filename) :-
string_term(FileString,Filename),
concat([FileString,$.DPL$],NewFilename),
open(Handle,NewFilename,r),
repeat,
get_term(Handle,Term),
rescind_previous_clauses(Term),
add_to_memory(Term),
Term == end_of_file,
close(Handle),
abolish(have_seen_this_predicate_before/2).
get_term(Handle,Term) :-
read(Handle,Term),
!.
get_term(_,end_of_file).
/****************************************************************
* *
* rescind_previous_clauses(Term) *
* checks to see if any term with the d-Prolog predicate of *
* Term has already been loaded. If so, or if we have reach- *
* ed the end of the file, nothing is done. Otherwise, the *
* d-Prolog predicate of Term is rescinded. Remember that *
* the d-Prolog predicate of a term may be different from *
* the Prolog predicate. For example, the Prolog prdicate of *
* 'neg flies(X) :- penguin(X)' is 'neg' and the Prolog pre- *
* dicate of 'flies(X) := bird(X)' is ':='. *
* *
***************************************************************/
rescind_previous_clauses(end_of_file) :- !.
rescind_previous_clauses(Term) :-
functor(Term,F,2),
member(F,[(:-),':=',':^']),
arg(1,Term,Head),
!,
rescind_previous_clauses(Head).
rescind_previous_clauses(incompatible(X,Y)) :-
!,
rescind_previous_clauses(X),
rescind_previous_clauses(Y).
rescind_previous_clauses('neg' Term) :-
!,
rescind_previous_clauses(Term).
rescind_previous_clauses(Term) :-
functor(Term,Predicate,Arity),
have_seen_this_predicate_before(Predicate,Arity),
!.
rescind_previous_clauses(Term) :-
functor(Term,Predicate,Arity),
make_dummy_clause(Arity,Predicate,Dummy),
rescind(Dummy),
asserta(have_seen_this_predicate_before(Predicate,Arity)).
add_to_memory(end_of_file) :- !.
add_to_memory(Term) :-
assertz(Term).
/****************************************************************
* *
* make_dummy_clause(N,[Predicate],Dummy) *
* produces a clause with Predicate as the functor and N *
* many variables as arguments. This is used with rescind *
* to eliminate clauses that are being reloaded. *
* *
****************************************************************/
make_dummy_clause(N,Predicate,Dummy) :-
make_variable_list(N,[],VariableList),
Dummy =.. [Predicate|VariableList],
!.
make_variable_list(0,X,X).
make_variable_list(N,OldList,VariableList) :-
M is N - 1,
make_variable_list(M,[_|OldList],VariableList).
/***************************************************************
* *
* redit will edit then reload a d-Prolog database. The same *
* restrictions on parameter and filename extension apply to *
* redit as to reload. *
* *
****************************************************************/
redit(Filename) :-
string_term(FileString,Filename),
concat([FileString,$.DPL$],NewFilename),
edit(NewFilename),
reload(Filename).